1/* Harry Potter and the Philosopher''s Stone 
    2    By Karthik Alle.
    3    Consult this file and issue the command: start. */
    4
    5:- dynamic at/2, i_am_at/1, did_not_speak/1, spoke/1, h_magic/1, magic/1, not_dead/1, not_stunned/1, not_transformed/1, can_stupefy_troll/1, can_stupefy/1, alohomora/0, not_disarmed/1. /* Needed by SWI-Prolog. */
    6
    7:- retractall(at(_, _)), retractall(i_am_at(_)), retractall(alive(_)), retractall(h_magic(_)), retractall(not_dead(_)),
    8    retractall(not_stunned(_)), retractall(can_stupefy_troll(_)), retractall(not_transformed(_)), retractall(not_stunned(_)),
    9    retractall(can_stupefy(_)).   10
   11/* This defines my current location. */
   12
   13i_am_at(gryffindor_fireplace).
   14
   15/* These facts describe how the rooms are connected. */
   16
   17path(gryffindor_fireplace, front, dumbledore).
   18path(gryffindor_fireplace, right, common_room_door) :- 
   19        did_not_speak(dumbledore),
   20        write('You cannot go out unless you speak to Dumbledore'), nl, !, fail.
   21
   22path(gryffindor_fireplace, right, common_room_door).
   23path(gryffindor_fireplace, left, my_room).
   24
   25path(dumbledore, left, my_room).
   26path(dumbledore, right, common_room_door).
   27
   28path(my_room, back, gryffindor_fireplace).
   29
   30path(common_room_door, front, great_hall).
   31path(common_room_door, left, strange_stairs).
   32path(common_room_door, back, gryffindor_fireplace) :-
   33    not_transformed(malfoy).
   34
   35path(common_room_door, back, gryffindor_fireplace) :-
   36    write('Only a Gryffindor can enter the house.'), nl,
   37    write('You are now Malfoy, you can only enter the Slytherin House.'), nl,!, fail.
   38
   39path(great_hall, back, common_room_door).
   40path(great_hall, front, slytherin_house) :- 
   41    not_transformed(malfoy), 
   42    write('Only a Slytherin can enter the house. Try the polyjuice potion in the potions room.'), nl, !, fail.
   43
   44path(great_hall, front, slytherin_house).
   45
   46path(great_hall, right, dumbledore_office) :-
   47    not_transformed(malfoy).
   48
   49path(great_hall, right, dumbledore_office) :-
   50    write('Only Harry can enter Dumbledore''s office. You are now Malfoy and can only enter the Slytherin House.'), nl, !, fail.
   51
   52path(great_hall, left, long_corridor).
   53
   54path(long_corridor, left, girls_washroom).
   55path(long_corridor, right, potions_room).
   56
   57path(potions_room, back, long_corridor).
   58path(girls_washroom, back, long_corridor).
   59
   60path(slytherin_house, back, great_hall) :- 
   61    assert(not_transformed(malfoy)), 
   62    write('You have transformed back to Harry!'), nl, nl.
   63
   64path(long_corridor, back, great_hall).
   65path(dumbledore_office, back, great_hall).
   66
   67path(strange_stairs, back, common_room_door).
   68
   69path(strange_stairs, front, locked_room) :-
   70        write('The door is locked'), nl,
   71        write('Perform the alohomora. Spell to open it.'), nl, !, fail.
   72
   73path(locked_room, front, trap_door) :- at(invisible_cloak, in_hand).
   74path(locked_room, right, death).
   75path(locked_room, left, death).
   76path(locked_room, back, strange_stairs).
   77
   78path(locked_room, front, trap_door) :- 
   79        write('Where is your cloak!?!'), nl, 
   80        write('You are not invisible, the dogs ate each of your heads off!'), nl, !, die.
   81
   82
   83path(trap_door, back, locked_room) :-
   84        write('You have climbed back to the room.'), nl.
   85
   86
   87path(trap_door, right, wizards_chess) :- 
   88        at(ron, in_hand),
   89        h_magic(X),
   90        X > 60,
   91        write('The chess game has begun and you have won! Thanks to Ron!'), nl,
   92        write('But you lost your magic by 60'), nl,
   93        decrease_magic_by(60),
   94        assert(at(magic_potion, wizards_chess)), !.
   95
   96
   97path(trap_door, right, wizards_chess) :-
   98        at(ron, in_hand),
   99        h_magic(X),
  100        X > 60,
  101        write('You don''t have enough Magic to play wizards chess'), nl, !, fail.
  102
  103path(trap_door, right, wizards_chess) :-
  104        write('You cannot play wizards_chess like Ron! You can never win this alone!'), nl, 
  105        write('He is kidnapped by the Slytherins, go rescue him!'), nl, !, fail.
  106
  107path(trap_door, back, trap_door).
  108
  109path(wizards_chess, front, last_chamber) :-
  110        (
  111            at(hermione, in_hand) ;
  112            at(ron, in_hand)
  113        ),
  114        write('Leave both Hermione and Ron if you want to fight Voldemort!'), nl, !, fail.
  115
  116path(wizards_chess, front, last_chamber).
  117
  118path(last_chamber, _, voldemort_kill).
  119
  120/* These facts tell where the various objects in the game
  121   are located. */
  122
  123at(wand, my_room).
  124at(hermione, girls_washroom).
  125at(ron, slytherin_house).
  126at(chest, dumbledore_office).
  127at(philosopher_stone, last_chamber).
  128
  129can_stupefy_troll(troll).
  130can_stupefy(vincent).
  131can_stupefy(gregory).
  132can_stupefy(voldemort).
  133
  134/* This fact specify that harry spoke to dumbledore */
  135
  136did_not_speak(dumbledore).
  137not_dead(troll).
  138not_transformed(malfoy).
  139not_stunned(gregory).
  140not_stunned(vincent).
  141not_stunned(voldemort).
  142not_disarmed(voldemort).
  143
  144magic(X) :-
  145    X is 100,
  146    assert(h_magic(X)), !.
  147
  148decrease_magic :-
  149    h_magic(X),
  150    Y is X - 10,
  151    retract(h_magic(_)),
  152    assert(h_magic(Y)), !.
  153
  154decrease_magic_by(Z) :-
  155    h_magic(X),
  156    Y is X - Z,
  157    retract(h_magic(_)),
  158    assert(h_magic(Y)),
  159    my_magic, !.
  160
  161my_magic :-
  162    h_magic(X),
  163    X < 0,
  164    write('You don''t have any magic left.'), nl, !.
  165
  166my_magic :-
  167    h_magic(X),
  168    write('Your magic is now '), write(X), nl, !.
  169
  170brew(magic_potion) :-
  171    retractall(h_magic(_)), 
  172    assert(h_magic(100)),
  173    write('Your magic has replenished to 100!'), nl, !.
  174
  175brew(polyjuice_potion) :-
  176    retract(not_transformed(malfoy)), write('You have now transformed to Malfoy.'), nl, 
  177    write('You will transform back to Harry only when you enter and exit the Slytherin House.'), !.
  178
  179alohomora :-
  180        at(hermione, in_hand),
  181        i_am_at(strange_stairs),
  182        h_magic(X),
  183        X < 20,
  184        write('You need 20 magic to perform alohomora.'), nl, !.
  185
  186alohomora :-
  187        at(hermione, in_hand),
  188        i_am_at(strange_stairs),
  189        h_magic(X),
  190        X > 20,
  191        decrease_magic_by(20),
  192        retractall(i_am_at(_)),
  193        assert(i_am_at(locked_room)),
  194        describe(locked_room), !.
  195
  196alohomora :-
  197        at(hermione, in_hand),
  198        i_am_at(dumbledore_office),
  199        h_magic(X),
  200        X < 20,
  201        write('You need 20 magic to perform alohomora.'), nl, !.
  202
  203alohomora :-
  204        at(hermione, in_hand),
  205        i_am_at(dumbledore_office),
  206        h_magic(X),
  207        X > 20,
  208        retract(at(chest, dumbledore_office)),
  209        assert(at(invisible_cloak, dumbledore_office)),
  210        write('There is the invisible cloak in the chest'), nl, !.
  211
  212alohomora :-
  213        at(hermione, in_hand),
  214        write('There is nothing here to open'), nl, !.
  215
  216alohomora :-
  217        write('You need hermione to teach you how to perform the spell'), nl.
  218
  219expelliarmus :-
  220        i_am_at(last_chamber),
  221        not_disarmed(voldemort),
  222        retractall(not_disarmed(_)),
  223        decrease_magic_by(70),
  224        write('You have disarmed Voldemort, now stupefy him.'), nl, !.
  225
  226expelliarmus :-
  227        i_am_at(last_chamber),
  228        write('You have disarmed Voldemort, now stupefy him.'), nl, !.
  229
  230expelliarmus :-
  231        i_am_at(last_chamber),
  232        decrease_magic_by(70),
  233        retractall(not_disarmed(_)),
  234        write('You have disarmed Voldemort, now stupefy him.'), nl, !.
  235
  236expelliarmus :-
  237        write('There is no weapon here to disarm.'), nl, !.
  238
  239stupefy(Y) :-
  240        at(wand, in_hand),
  241        i_am_at(last_chamber),
  242        not_disarmed(Y),
  243        write('Wrong spell! Voldemort peformed the Avada Kedavra and you are dead!'), nl, !, die.
  244
  245stupefy(Y) :-
  246        at(wand, in_hand),
  247        i_am_at(last_chamber),
  248        can_stupefy(Y),
  249        decrease_magic_by(30),
  250        retract(not_stunned(Y)),
  251        assert(stunned(Y)),
  252        write('Your stun spell hit Voldemort and he Disapparated!'), nl, !.
  253
  254stupefy(Y) :-
  255        at(wand, in_hand),
  256        can_stupefy_troll(Y),
  257        not_dead(troll),
  258        i_am_at(girls_washroom),
  259        h_magic(M),
  260        M < 70,
  261        write('You need 70 magic to stun the Troll!'), nl, !.
  262
  263stupefy(Y) :-
  264        at(wand, in_hand),
  265        can_stupefy_troll(Y),
  266        i_am_at(girls_washroom),
  267        not_dead(troll),
  268        retract(not_dead(troll)),
  269        write('The troll was stunned!'), nl,
  270        decrease_magic_by(70), !.
  271
  272stupefy(Y) :-
  273        at(wand, in_hand),
  274        can_stupefy_troll(Y),
  275        i_am_at(slytherin_house),
  276        h_magic(M),
  277        M < 30,
  278        write('You need 30 magic to stun '),write(Y),write('!'), nl, !.
  279
  280stupefy(Y) :-
  281        at(wand, in_hand),
  282        can_stupefy(Y),
  283        i_am_at(slytherin_house),
  284        retract(not_stunned(Y)),
  285        assert(stunned(Y)),
  286        write(Y),write(' was stunned!'), nl,
  287        decrease_magic_by(30), !.
  288
  289stupefy(Y) :-
  290        at(wand, in_hand),
  291        write('There is no '), write(Y), write(' here to stupefy.'), nl, !.
  292
  293stupefy(_) :-
  294        write('You need a wand to perform spells'), nl, !.
  295
  296/* These rules describe how to pick up an object. */
  297
  298take(X) :-
  299        i_am_at(dumbledore_office),
  300        X = chest,
  301        write('You cannot take the chest, Perform the alohomora. spell to open it.'), nl, !.
  302
  303take(_) :-
  304        i_am_at(last_chamber),
  305        not_stunned(voldemort),
  306        write('You cannot take the stone when Voldemort is there'), nl, !.
  307
  308take(_) :-
  309        i_am_at(last_chamber),
  310        write('Well done Harry! You have retrieved the philosopher''s stone'), nl, finish, !.
  311
  312take(_) :-
  313        i_am_at(wizards_chess),
  314        brew(magic_potion),
  315        retract(at(magic_potion, wizards_chess)),
  316        write('You drank the potion and your magic is replenished.'), nl, !.
  317
  318take(_) :-
  319        i_am_at(girls_washroom),
  320        not_dead(troll),
  321        write('First stupefy the troll and then take Hermione!'), nl, !.
  322
  323take(_) :-
  324        i_am_at(slytherin_house),
  325        not_stunned(vincent),
  326        not_stunned(gregory),
  327        write('Stupefy Vincent and Gregory and then take Ron!'), nl, !.
  328
  329take(_) :-
  330        i_am_at(slytherin_house),
  331        not_stunned(vincent),
  332        write('Stupefy Vincent and then take Ron!'), nl, !.
  333
  334take(_) :-
  335        i_am_at(slytherin_house),
  336        not_stunned(gregory),
  337        write('Stupefy Gregory and then take Ron!'), nl, !.
  338
  339take(X) :-
  340        at(X, in_hand),
  341        write('You''re already holding it!'),
  342        nl, !.
  343
  344take(X) :-
  345        i_am_at(Place),
  346        at(X, Place),
  347        retract(at(X, Place)),
  348        assert(at(X, in_hand)),
  349        write('OK.'),
  350        nl, !.
  351
  352take(_) :-
  353        write('I don''t see it here.'),
  354        nl.
  355
  356/* These rules describe how to put down an object. */
  357leave(X) :-
  358        drop(X).
  359
  360drop(X) :-
  361        at(X, in_hand),
  362        i_am_at(Place),
  363        retract(at(X, in_hand)),
  364        assert(at(X, Place)),
  365        write('OK.'),
  366        nl, !.
  367
  368drop(_) :-
  369        write('You aren''t holding it!'),
  370        nl.
  371
  372inventory :- 
  373        write('You have the following in your inventory:'), nl,
  374        list_inventory.
  375
  376list_inventory :-
  377        at(X, in_hand),
  378        write(X), nl,
  379        fail.
  380
  381list_inventory :-
  382        write(''), nl.
  383
  384/* These rules define the six direction letters as calls to go/1. */
  385
  386front :- go(front).
  387
  388back :- go(back).
  389
  390right :- go(right).
  391
  392left :- go(left).
  393
  394i :- inventory.
  395
  396/* This rule tells how to move in a given direction. */
  397
  398go(Direction) :-
  399        i_am_at(Here),
  400        path(Here, Direction, There),
  401        retract(i_am_at(Here)),
  402        assert(i_am_at(There)),
  403        look, !.
  404
  405go(_) :-
  406        write('You can''t go that way.').
  407
  408
  409/* This rule tells how to look about you. */
  410
  411look :-
  412        i_am_at(Place),
  413        describe(Place),
  414        nl,
  415        notice_objects_at(Place), !.
  416
  417
  418/* These rules set up a loop to mention all the objects
  419   in your vicinity. */
  420
  421notice_objects_at(Place) :-
  422        at(X, Place),
  423        write('There is '), write(X), write(' here.'), nl,
  424        fail.
  425
  426notice_objects_at(_).
  427
  428/* This rule tells how to die. */
  429
  430die :-
  431        !, finish.
  432
  433
  434/* Under UNIX, the   halt.  command quits Prolog but does not
  435   remove the output window. On a PC, however, the window
  436   disappears before the final output can be seen. Hence this
  437   routine requests the user to perform the final  halt.  */
  438
  439finish :-
  440        nl,
  441        write('The game is over. Please enter the halt. command.'),
  442        nl, !.
  443
  444
  445/* This rule just writes out game instructions. */
  446
  447instructions :-
  448        nl,
  449        write('Enter commands using standard Prolog syntax.'), nl,
  450        write('Available commands are:'), nl,
  451        write('start.                           -- to start the game.'), nl,
  452        write('front. back. right. left.        -- to go in that direction.'), nl,
  453        write('cast(Spell, On).                 -- to cast a spell on someone'), nl,
  454        write('spells.                          -- to see list of your spells.'), nl,
  455        write('take(Object).                    -- to pick up an object.'), nl,
  456        write('drop(Object). or leave(Object).  -- to put down an object.'), nl,
  457        write('i. or inventory.                 -- to check your inventory.'), nl,
  458        write('my_magic.                        -- to check how much magic is left.'), nl,
  459        write('look.                            -- to look around you again.'), nl,
  460        write('instructions.                    -- to see this message again.'), nl,
  461        write('halt.                            -- to end the game and quit.'), nl,
  462        nl, nl,
  463        write('Make sure you check your magic from time to time.'), nl, nl.
  464
  465/* This rule prints out instructions and tells where you are. */
  466
  467start :-
  468        instructions,
  469        write('Hello Harry Potter, Welcome to Hogwarts! You are at the Gryffindors Fireplace.'), nl,
  470        magic(_),
  471        look,
  472        write('Your magic is 100. Brew magic potion at the potions room to replenish your magic'), nl, nl.
  473
  474/* These rules describe the various rooms.  Depending on
  475   circumstances, a room may have more than one description. */
  476
  477spells :-
  478        write('stupefy(X).          -- The Stunning Spell that renders a victim unconscious.'), nl,
  479        write('expelliarmus.        -- Unlocks and opens doors and windows.'), nl,
  480        write('alohomora.           -- A charm that unlocks and opens doors and windows'), nl.
  481
  482describe(gryffindor_fireplace) :-
  483        did_not_speak(dumbledore),
  484        at(wand, in_hand),
  485        write('Dumbledore is standing by the fire infront of you and has been waiting to talk to you.'), nl,
  486        write('Your room is to the left.'), nl,
  487        write('If you want to go out of the Gryffindor Commons, the exit is to the right.'), nl, !.
  488
  489describe(gryffindor_fireplace) :-
  490        did_not_speak(dumbledore),
  491        write('Dumbledore is standing by the fire infront of you and has been waiting to talk to you.'), nl,
  492        write('Your room is to the left, where your wand must be!'), nl,
  493        write('If you want to go out of the Gryffindor Commons, the exit is to the right.'), nl.
  494
  495describe(gryffindor_fireplace) :-
  496        at(wand, in_hand),
  497        write('Dumbledore has vanished!'), nl,
  498        write('Your room is to the left.'), nl,
  499        write('If you want to go out, the exit is to the right.'), nl, !.
  500
  501describe(gryffindor_fireplace) :-
  502        write('Dumbledore has vanished!'), nl,
  503        write('Your room is to the left, where you must have forgot your wand.'), nl,
  504        write('If you want to go out, the exit is to the right.'), nl.
  505
  506describe(dumbledore) :-
  507        retract(did_not_speak(dumbledore)),
  508        assert(spoke(dumbledore)),
  509        assert(at(deluminator, gryffindor_fireplace)),
  510        retractall(i_am_at(_)),
  511        assert(i_am_at(gryffindor_fireplace)),
  512        write('Harry Potter, I have a dangerous task for you boy!'), nl,
  513        write('You need to retrieve the Philosopher''s stone before it falls into the wrong hands.'), nl,
  514        write('Use all the magic you have learnt. But use them carefully, as you have limited magic power.'), nl,
  515        write('Remember to always hold your friends.'), nl,
  516        write('These are dark times Harry, really dark times!'), nl, !.
  517
  518describe(dumbledore) :-
  519        describe(gryffindor_fireplace).
  520
  521describe(my_room) :-
  522        at(wand, in_hand), !, write('Ron is not in your room, wonder where he is!'), nl.
  523
  524describe(my_room) :-
  525        write('Ron is not in your room, wonder where he is!'), nl,
  526        write('To perform magic, you need your wand.'), nl.
  527
  528describe(common_room_door) :-
  529        write('You are infront of the Gryffindor''s Common Door, with the fat lady staring at you.'), nl,
  530        write('Turn back if you want to enter the Gryffindor''s Common'), nl,
  531        write('Go front towards the Great Hall.'), nl,
  532        write('There is a mysterious stairs leading to an old door to your left.'), nl,
  533        write('It was never there before, maybe it leads to the Philosopher''s stone.'), nl.
  534
  535describe(strange_stairs) :-
  536        write('You are infront of an old door! It seems to be locked.'), nl,
  537        write('You can go front and perform the alohomora. Spell.'), nl,
  538        write('You can go back to your Gryffindor common room door.').
  539
  540describe(great_hall) :-
  541        write('You are at the great hall is lit by thousands and thousands of candles.'), nl,
  542        write('Straight ahead is the path to Slytherin''s house.'), nl,
  543        write('To your left is a long corridor.'), nl,
  544        write('To your right is the Gargoyle Corridor that leads to Dumbledore''s Office.'), nl, nl,
  545        write('Turn back if you want to go to Gryffindor''s Commons'), nl, nl,
  546        describe(neville).
  547
  548describe(neville) :-
  549        not_transformed(malfoy),
  550        at(hermione, in_hand),
  551        at(ron, in_hand),
  552        write('Neville Longbottom says ''Good that you saved both! Now go get the stone.'''), nl.
  553
  554describe(neville) :-
  555        not_transformed(malfoy),
  556        at(hermione, in_hand),
  557        write('Neville Longbottom says'), nl,
  558        write('''Good that you saved Hermione.'),nl,
  559        write('Ron has been kidnapped by Malfoy! He must be in the Slytherin''s House'''), nl.
  560
  561describe(neville) :-
  562        not_transformed(malfoy),
  563        at(ron, in_hand),
  564        write('Neville Longbottom says'), nl,
  565        write('''Good that you saved Ron.'), nl,
  566        write('I heard that Hermione has been crying all day in the girls washroom.'''), nl.
  567
  568describe(neville) :-
  569        not_transformed(malfoy),
  570        write('Neville Longbottom runs to you and says'),nl, 
  571        write('''Hey Harry! I heard that Hermione has been crying all day in the girls washroom.'), nl, 
  572        write(' And Ron has been kidnapped by Malfoy! He must be in the Slytherin''s House'''), nl.
  573
  574describe(neville).
  575
  576describe(slytherin_house) :-
  577        not_stunned(vincent),
  578        not_stunned(gregory),
  579        write('You are inside the Slytherin House.'), nl,
  580        write('Vincent and Gregory are guarding Ron.'), nl,
  581        write('Stupefy each of them and rescue Ron!'), nl.
  582
  583describe(slytherin_house) :-
  584        not_stunned(vincent),
  585        write('You are inside the Slytherin House.'), nl,
  586        write('Vincent is guarding Ron, while Gregory is in a stunned state.'), nl,
  587        write('Stupefy Vincent rescue Ron!'), nl.
  588
  589describe(slytherin_house) :-
  590        not_stunned(gregory),
  591        write('You are inside the Slytherin House.'), nl,
  592        write('Gregory is guarding Ron, while Vincent is in a stunned state.'), nl,
  593        write('Stupefy Gregory and rescue Ron!'), nl.        
  594
  595describe(slytherin_house) :-
  596        write('You are inside the Slytherin House.'), nl,
  597        write('Vincent and Gregory are in a stunned state'), nl.
  598
  599describe(dumbledore_office) :-
  600        at(deluminator, in_hand),
  601        write('There are a vast number of portraits of past headmasters, all evidently asleep.'), nl.
  602
  603
  604describe(dumbledore_office) :-
  605        write('The Office is too dark, you can''t see anything.'), nl,
  606        write('Dumbledore must have left his deluminator when he vanished.'), nl,
  607        write('Go Pick it Up!'), nl, fail.
  608
  609describe(potions_room) :-
  610        write('You can brew potions, following specific recipes and using ingredients.'), nl,
  611        write('brew(magic_potion). to heal your magic power.'), nl,
  612        write('brew(polyjuice_potion). to turn into Malfoy so that you can enter the Slytherin House.'), nl,
  613        write('Once you are done, go back to the Long Corridor').
  614
  615describe(long_corridor) :-
  616        at(hermione, in_hand),
  617        write('You have reached the end of corridor.'), nl,
  618        write('There is the girls washroom to your right.'), nl,
  619        write('The potions room to your right.'), nl,
  620        write('Turn back to go to the Great Hall.').
  621
  622describe(long_corridor) :-
  623        write('You have reached the end of corridor.'), nl,
  624        write('A troll is eventually making its way from the dungeons up to the first floor, heading into the girls bathroom to your left. Rescue hermione!'), nl,
  625        write('There is the potions room to your right.'), nl,
  626        write('Turn back to go to the Great Hall.').
  627
  628describe(girls_washroom) :-
  629        not_dead(troll),
  630        write('The troll is attacking hermione! Cast a spell on the troll and save her!'), nl, !.
  631
  632describe(girls_washroom) :-
  633        at(hermione, in_hand),
  634        write('The girls washroom is empty.'), nl, !.
  635        
  636describe(girls_washroom) :-
  637        write('You are at the girls washroom'), nl.
  638
  639describe(locked_room) :-
  640        at(invisible_cloak, in_hand),
  641        write('Stand still! There is a three headed dog sleeping infront of you.'), nl,
  642        write('One wrong step and you are dead!'), nl, nl,
  643        write('There is a trap door in front of you, enter quietly.'), nl,
  644        write('Go back if you want to exit to the strange stairs.'), nl.
  645
  646describe(locked_room) :-
  647        write('Stand still! There is a three headed dog sleeping infront of you.'), nl,
  648        write('There is a trap door infront of you.'), nl,
  649        write('You need to be invisible to enter the trap door.'), nl,
  650        write('Make a wrong step and you are dead!'), nl,
  651        write('Go back quitely to the strange stairs.'), nl.
  652
  653describe(trap_door) :-
  654        write('To your right is the wizards chess.'), nl,
  655        write('Turn back if you want to slide up the trap door'), nl.
  656
  657describe(death) :-
  658        at(invisible_cloak, in_hand),
  659        write('Even though you are invisible, you are noisy.'), nl,
  660        write('The dogs woke up and ate you!'), !, die.
  661
  662describe(wizards_chess) :-
  663        write('There is all rumble over the floor after the chess game.'), nl,
  664        write('In front of you is the last chamber, and you can hear Voldemort''s Voice from inside'), nl,
  665        write('It is really dangerous to take Hermione and Ron with you inside that door.'), nl, !.
  666
  667describe(last_chamber) :-
  668        not_disarmed(voldemort),
  669        not_stunned(voldemort),
  670        write('There is Voldemort holding his wand at you and yelling:'), nl,
  671        write('''Harry Potter, the boy who lived! You cannot take the stone when I am here!'''), nl, nl,
  672        write('Disarm him using the expelliarmus. charm or he will kill you.'), nl,
  673        write('Do something else and you are dead!'), nl.
  674
  675describe(last_chamber) :-
  676        not_disarmed(voldemort),
  677        write('Stupefy Voldemort and take the stone.'), nl,
  678        write('Do something else and you are dead!'), nl.
  679
  680describe(last_chamber) :-
  681        write('Take the philosopher''s stone to win the game!'), nl.
  682
  683describe(voldemort_kill) :-
  684        write('Wrong Move! Voldemort peformed the Avada Kedavra and you are dead!'), nl, die, !